perm filename LOSS.1[COM,LSP] blob sn#828442 filedate 1986-11-16 generic text, type C, neo UTF8
COMMENT āŠ—   VALID 00011 PAGES
C REC  PAGE   DESCRIPTION
C00001 00001
C00002 00002	common-lisp-object-system/su
C00007 00003	common-lisp-object-system/su
C00013 00004	Remarks on Generic Functions
C00020 00005	Remarks on Generic Functions
C00043 00006	/sub
C00050 00007	Class Precedence List
C00054 00008	\ssect{Number of Namespaces}
C00057 00009	/sub
C00059 00010	A {\bf namespace} is a sub-environment in which the nature of the objects to
C00060 00011	/sub
C00073 ENDMK
CāŠ—;
common-lisp-object-system/su
Anonymous Generic Function Proposal

Here are a series of proposals for making anonymous generic functions
in a pleasant way. There are three sorts of non-named-by-symbol generic
function forms we need to define: pure anonymous, LABELS equivalent, and
FLET equivalent. There is probably only one reasonable way to define
anonymous generic functions:

#'(generic-lambda <method-spec>*)

where <method-spec> is

	(<qualified lambda list> . <body>)

For example:

#'(generic-lambda
   (((x1 c1)(x2 c2)) (foo x1 x2))
   (((x1 c3) (x2 c4)) (baz x1 x2)))

The two remaining cases are for LABELS and FLET equivalents.
GENERIC-FUNCTION-LABELS corresponds to LABELS and GENERIC-FLET corresponds
to FLET. These names are negotiable.

For each of GENERIC-FUNCTION-LABELS and GENERIC-FLET there are two
possible styles, called the modular and the distributed styles. In the
modular style:

(generic-function-labels (<generic-function-spec>*) . <body>)

where <generic-function-spec> is

(<generic-function-name> <method-spec>*)

where the <method-spec> is as above. Here is an example:

(generic-function-labels
 ((gf1
   ;;; First method on gf1
   (((x1 c1) (x2 c2)) (when (recursivep x1) (gf1 (f1 x1) (f2 x2))))
   ;;; Second method on gf1
   (((x1 c3) (x2 c3)) (when (recursivep x1) (gf2 (f3 x1) (f4 x2)))))
  (gf2
   ;;; First method on gf2
   (((x1 c4)(x2 c5)) (gf1 (f5 x1) (f6 x2)))
   ;;; Second method on gf2
   (((x1 c6)(x2 c7)) (gf2 (f7 x1)(f8 x2)))))
 ;;; Now we use these guys
 (gf1 x1 y1) ... (gf2 xn yn))

The distributed style looks like this:

(generic-function-labels (<named-method-spec>*) . <body>)

where <named-method-spec> is

(<generic-function-name> <method-spec>)

Here is an example:

(generic-function-labels
 ;;; First method on gf1
 ((gf1 ((x1 c1) (x2 c2)) (when (recursivep x1) (gf1 (f1 x1) (f2 x2))))
  ;;; Second method on gf1
  (gf1 ((x1 c3) (x2 c3)) (when (recursivep x1) (gf2 (f3 x1) (f4 x2))))
  ;;; First method on gf2
  (gf2 ((x1 c4)(x2 c5)) (gf1 (f5 x1) (f6 x2)))
  ;;; Second method on gf2
  (gf2 ((x1 c6)(x2 c7)) (gf2 (f7 x1)(f8 x2))))
 ;;; Now we use these guys
 (gf1 x1 y1) ... (gf2 xn yn))

The GENERIC-FLET admits both modular and distributed styles, which
I won't show.

I'm not sure which I favor. Of course, one can ADD-METHOD to any of
these generic functions.

I made an assumption when devising these, which was that it is not
possible for a method to call another method without the intervention
of a generic function.  In this case, a hairier reference scheme is
needed.

			-rpg-
common-lisp-object-system/su
Anonymous Generic Function Proposal (con't)

Hm, if I didn't know better, I'd say that people's opinions of an idea are
strongly related to whether they thought of it or whether they would have
thought of them.

First, it is possible to create anonymous generic functions using
MAKE-GENERIC and ADD-METHOD. This was pointed out already.  Unlike
anonymous functions, it is relatively easy to make self-referential
generic functions using the above functions and FUNCALL. One can make
self-referential anonymous functions in Common Lisp with FUNCTION and
FUNCALL, but using the Y function (definition below).  If we want to
discourage people from making anonymous generic functions, then the ploy
of providing only MAKE-GENERIC, ADD-METHOD, and FUNCALL is a good
approach. Here is an example:

;;; I use MOON'S CONVENTION for code capitalization

(LET ((GF (MAKE-GENERIC)))
 (ADD-METHOD GF '((X C1)(Y C2)) #'(LAMBDA (X Y) ...))
 (FUNCALL GF ...))

If I want the methods of GF to refer to GF itself, I have to FUNCALL
the value of GF inside the #'(LAMBDA ...).

Of course, when X3J13 decides to flush the function cell, things
will look a lot nicer, because then the random FUNCALLs will go away.
Mutually referential generic functions, though, will still be difficult.
Although, I guess, we can use Y. Generic functions will be slow enough that
the performance loss won't make much difference.

Second, the question has been raised about when people will want to
use such a thing as an anonymous generic function. There are several
remarks to be made about this point. A programming style that I think
is reasonable is to take functions, pack them into data structures, and
FUNCALL them at various times. To do this requires anonymous generic functions,
and unless there is decent syntax, analagous to the syntax for doing the
same things for anonymous functions, people will be discouraged from doing it.
I think this will lead people into using DEFMETHOD and doing #', which can
lead to method leakage, because there will be these irrelevant symbols
to contend with. Using GENERIC-FUNCION-LET the user can be sure that
the methods invoke the intended generic functions, regardless of any
screwing around with symbols (this is precisely what LABELS buys you
in the function world).

Third, people have stated that the reasonable programming style is to
spray DEFMETHODs all over the place. My proposal does not change the syntax
for DEFMETHOD, it doesn't discourage that style, it simply offers another
style. If modularzing in-the-medium by defining methods is a good programming
style, then why isn't it good style to write a smaller set of methods
in a closed world? Is it bad style all of a sudden?

Fourth, the exercise of defining the complete set of cases for generic
functions forces us and readers of the documentation to think about
what a generic function really is. Methods are associated with functions,
not with classes. This is one of the new ideas in CommonLoops, and it is
worth following that idea to its logical conclusion. I believe the
reason that the non-Symbolosians did not favor special classical method
syntax is that it confused the user on this point - classical method
syntax implies methods attached to classes, multi-methods implies methods
attached to generic functions.


Remarks on Generic Functions

I still believe that there is misunderstanding about the nature
of generic functions. I think it is a mistake for anyone to believe
that the current implementation of PCL represents any committment
to the nature of generic functions as put forward by this working
group, nor does that implementation imply anything about the
beliefs of Danny, Gregor, or myself regarding their nature.

Because Moon gets a bad rash when he reads imprecise language
and because when he reads it he tends to waste a lot of time
thinking about what the author could mean - he never succeeds
or only seems to be able to guess absurd possibilities - I will
write a simple formal description of the things about which
I believe we agree. Furthermore, I will outline in formal terms
the possible decisions we can make.

The idea is to model the operation of a non-multiprogrammed or
non-multitasked Lisp as a sequence of states, where there is some
base state (the Lisp when it is first initialized) and where 
each state in the sequence yields the next state by means of a
Lisp operation.

First some notation.

ADDRESSES is the set of all Lisp addresses.

ROOT is the set of Lisp roots (pointers).

A state is an address space. A state will be written
as Ai, for i in the non-negative integers. (A0, A1, ...)

POINTERS(A) is the set of all Lisp pointers in the address space, A, of
the Lisp.

OBJECTS(A) is the set of all Lisp objects in the address space, A, of
the Lisp.

Note that the set of pointers and objects is indexed by an address
space. When the address space in question is irrelevant, we will
drop the index.

OBJECT(x) is a function from POINTERS to OBJECTS, which, for any pointer, x,
in POINTERS yields the Lisp object in OBJECTS to which the pointer points.

POINTS(x,y), x in POINTERS, y in OBJECTS, is a relation between
POINTERS and OBJECTS such that POINTS(x,y) is true if and only if
y=OBJECT(x).

S-POINTS(s1,s2) where s1 is a subset of POINTERS and s2 is a subset
of OBJECTS, is a relation between sets of POINTERS and sets of OBJECTS
such that S-POINTS(s1,s2) is true if and only if the following two
situations obtain:

	1. for every x in s1 there exists a y in s2 such that
	   POINTS(x,y)

	2. for every y in s2 there exists an x in s1 such that
	   POINTS(x,y)

L-POINTERS(o) is a function from OBJECTS to the power set of POINTERS
such that L-POINTERS(o) is the set of Lisp pointers in the Lisp object,
o. For example, L-POINTERS(<cons cell>) is the set consisting of the
CAR and the CDR cells.

RAW-STORAGE(o) is the set of storage (addresses) used by the object, o.

O-OBJECTS(o) is a function from objects to the power set of OBJECTS
such that 

O-OBJECTS(o) = [o in OBJECTS | there exists an x in L-POINTERS(o)
                               and o = POINTS(x)]

That is, this set is obtained by collecting for each pointer, x, the
object, o, to which x points.

POINTS*(p) is a function from POINTERS to the power set of OBJECTS
such that

POINTS*(p) = [o in OBJECTS | o is in the transitive closure of
			     OBJECT(p) under O-OBJECTS]

This corresponds to the set of all objects accessible from p by pointer
tracing. 

ALIVE(A) is the subset of POINTERS(A) that is the union of POINTS*(r), r
in ROOTS. The pointers in POINTERS(A)-ALIVE(A) represent storage available
for garbage collection.

Consider the sequence of address spaces, A0, ...
We define EVAL(e,a) to be a function from Lisp expressions and
address spaces such that A(i+1)=EVAL(e,Ai) if A(i+1) is the
address space the results from evaluating the expression e in
the address space Ai. This is not as formal as it could be.
It is understood that e is a Common Lisp expression, that Ai is
in the transitive closure of A0, a valid initial Lisp address space,
under EVAL ranging over all valid Common Lisp expressions.

CHANGED(A,e) is the set of pointers that either changed when e
is evaluated or added when e is evaluated. 
Remarks on Generic Functions

This long note contains some remarks addressed to the comments made
regarding generic functions. I think that people on this list do not share
the same ultimate view of what generic functions are and how they can be
used.

To me there are 3 things that the concept of generic functions buys us:

	1. The ability to spread the definition of a generic function
	   among the places where the partial definitions make the most
	   sense.  This is accomplished by placing DEFMETHODs in the
	   places where the relevant classes are defined, for example.

	2. The ability to abstract the definition of a generic function
	   into parts (methods) that are conceptually independent.  This
	   is accomplished by splitting the definition of a generic
	   function into independent parts where each part is the partial
	   function definition for a particular set of classes - each part
	   is a method.  This leads to a new modularization technique.

	3. The separation of the inheritance of behavior from placement of
	   code. Generic functions select methods based on the structure
	   of the class lattice, but the generic functions are not
	   contrained to be stored within that lattice.

Up until now I've only seen a deep appreciation of the first point by
members of this working group. I think this is natural because the only
experience that members of this working group have had is with
DEFMETHOD-like generic function definition.

Here is a summary of what I take to be our understanding of the nature of
generic functions.

There is a new type of first-class object, called a `generic function.'
It can be FUNCALLed and APPLYed exactly as Common Lisp functions can be.
When the function cell of a symbol contains a generic function, we say
that the symbol, call it S, `names' the generic function and that the
generic function is associated with the name, S. [This is exactly as
things are in Common Lisp with respect to functions.] Using MAKE-GENERIC
it is possible to create a generic function not associated with any
symbol.

Generic functions have internal structure. This internal structure
includes the argument list, the argument precedence order, method
combination information, and `methods.'  Not required in that internal
structure is a `name' for the generic function.  A generic function, in
some implementations, might have a name as part of itself but only as an
informational device for use by programming environment tools. The correct
functioning of generic function cannot depend on that name.  When a
generic function is invoked, it invokes and combines some subset of the
methods. Which methods are invoked and how their results are combined
depends on the classes of the arguments supplied to the generic function
and on the method combination type of the generic function.

Methods are objects with, possibly, some internal structure - this has not
yet, I believe, been decided.  Methods include a function, called the
`method function,' and possibly some other user-visible information.  One
such possible part of the internal structure might be a pointer back to
the generic function of which the method is part.  The term `method' is
commonly used to refer to method objects.

Methods are associated with generic functions, but are not associated
directly with any names except in an informational sense - the correct
functioning of a method cannot depend on its name.  If a method is part of
a generic function which is associated with a symbol, S, we say that the
method is `defined for S.'  ADD-METHOD and GET-METHOD add methods to and
retrieve method objects from, respectively, generic functions. DEFMETHOD
adds a method to the generic function associated with the symbol that is
the first argument of DEFMETHOD.

Methods are possibly applicable objects - I don't believe this has been
decided yet.

(typep <generic-function> 'function) 

returns T, and possibly 

(typep <method-object> 'function)

does too. It is certainly possible to write the following code:

(labels ((f (x) ...g...)  ;calls g
	 (g (x) ...h...)  ;calls h
	 (h (x) ...f...)) ;calls f
 (add-method <gf> '((x c1)) #'f)
 (add-method <gg> '((x c2)) #'g)
 (add-method <gh> '((x c3)) #'h))

where <gf>, <gg>, and <gh> are generic functions. This defines
a set of methods whose method functions are mutually referential.
This does not imply that methods are directly invocable.

Generic functions are self-contained objects.  The parts of generic
functions are not spread out in the heap, in tables, or in the class
lattice: The parts are contained in the generic function. Pointers to
generic functions might appear in various places for the proper function
of tools.  One place is the class lattice, which defines the inheritance
structure on which the operation of generic functions depends. [Note:
an implementation is free to spread the definition wherever it likes
as long as it maintains the illusion of generic functions as first-class
objects.]

For example, environmental tools for associating methods with classes are
desirable.  These tools will enable us to browse through a class lattice
and display all methods that operate on instances of the classes being
browsed.  To do this, the tool must be able to determine for each class
the generic functions that operate on that class.  In the case where a
generic function is associated with a symbol, it is nice to display that
symbol as the name of the generic function (that is, as the operator).

FMAKUNBOUND can disrupt the correct functioning of this tool.
FMAKUNBOUND, when applied to a symbol with which a generic function is
associated, removes the generic function definition from the function cell
of the symbol.  FMAKUNBOUND cannot cause generic functions to behave
inconsistently with respect to their invocation semantics. 
[(SETF (SYMBOL-FUNCTION ...) ...) also cannot disrupt invocation semantics.]

Let's look at an example. Suppose the user writes

(DEFMETHOD FOO ((X C)) ...)

The tool that displays generic functions for the class C will undoubtedly
display FOO by name. What does the class C store? It can store only the
symbol, FOO, or it can store not only the symbol, FOO, but also the
generic function stored in FOO's function cell.  If the user does
(FMAKUNBOUND 'FOO) and the symbol alone is stored with the class, the tool
might display the wrong thing; if the user then does a second DEFMETHOD on
FOO, then the tool will very likely display the wrong thing. If the class
stores the symbol and the generic function, the tool can, after the
FMAKUNBOUND, display the anonymous generic function without the associated
name, FOO - assuming mutability of generic functions.

Possibly there needs to be a function whose name could be
REMOVE-GENERIC-FUNCTION-FROM-CLASS-LATTICE which removes from the class
lattice all references to this generic function. The primary client of
this function will be environment tools.

Here is an example of some behavior I'd expect to see:

(DEFMETHOD FOO ((X C)) (FORMAT T "FOO, version 1, called on ~S~%" X))

<request to show the methods on C displays #<GENERIC-FUNCTION FOO>
and #<METHOD-OBJECT FOO> or something like that>
 
(FOO X) ;X an instance of C

causes

FOO, version 1, called on <X>

to be printed.

(SETQ BAZ #'FOO)

(FMAKUNBOUND 'FOO)

<request to show the methods on C displays #<GENERIC-FUNCTION 7128161>
and #<METHOD-OBJECT 86018603> or something like that>
 
(FOO X) ;X an instance of C

signals an error.

(DEFMETHOD FOO ((X C)) (FORMAT T "FOO, version 2, called on ~S~%" X))

<request to show the methods on C displays #<GENERIC-FUNCTION 7128161>
and #<METHOD-OBJECT 86018603> or something like that, and
#<GENERIC-FUNCTION FOO> and #<METHOD-OBJECT FOO> or something like that>

(FOO X) ;X an instance of C

causes 

FOO, version 2, called on <X>

and nothing else, to be printed.

(FUNCALL BAZ X) ;same X

causes

FOO, version 1, called on <X>

(SETQ BAZ NIL)

results in a situation in which the tool displays things that might
confuse the user. At this point the user might like to clean up the
environment

Now let's turn our attention to naming. Suppose someone writes:

;;; Define a recursive generic function
(DEFMETHOD FOO ((X C)) 
 ;; Do something useful
 (MUNCH X)
 ;; Do something related on a related class.
 (FOO (SOME-OTHER-CLASS X)))

(SETF (SYMBOL-FUNCTION 'BAZ) #'FOO)

(DEFMETHOD FOO ((X C1)) ...)

Oh dear, (BAZ <c, an instance of C>) might lose because the recursive call
in FOO refers to some other generic function than the one supposedly
intended when the code for the first DEFMETHOD on FOO was written.  Well,
we face the same problem with normal functions, and LABELS is used to
solve that:

(DEFUN FACT (N)
 (LABELS ((FACT (N) (IF (ZEROP N) 1 (* N (FACT (1- N))))))
  (FACT N)))

(FACT 47)
258623241511168180642964355153611979969197632389120000000000 

(SETF (SYMBOL-FUNCTION 'BAZ) #'FACT)

(DEFUN FACT (X)
 (FORMAT T "Adding ~S as a fact to the database!~% X)
 (ADD-FACT X)
 T)

(BAZ 47)
258623241511168180642964355153611979969197632389120000000000 

We should be able to define generic functions and methods that have this
degree of insulation from the accidents of naming.  Unless we define
something like GENERIC-FUNCTION-LABELS, the definition of such
self-contained generic functions will be ugly, containing FUNCALLs.

Some people have questioned whether it is a reasonable style to
write methods locally when it is clear that the intended purpose
of the standard is to let people write DEFMETHODs all over the place.

At the start of this message I mentioned several important things that
generic functions buy us. I will now paraphrase and expand on point number
2 above:


	   The concept of generic functions gives us the ability to
	   formulate the definition of a generic function as the
	   accumulation of methods, each modularly defined and each
	   specifically applicable to a set of classes. This enables the
	   programmer to formulate his code in natural pieces and to have
	   them assembled by the generic-function-calling mechanism.

The point behind my `lexically defined generic function' proposal is to
recognize and promulgate this programming methodology.  If it is a good
methodolgy to define generic functions that are associated with symbols
using this modular approach, then it should be a good methodology to
define anonymous generic functions the same way.  Using MAKE-GENERIC and
ADD-METHOD it is possible to do this, but at the expense of unreadable
code.

There is a second sort of `local' definition of methods that could make
sense - it is the one to which Gregor alluded in his message about my
anonymous generic function proposal. Suppose that a set of methods on the
symbol, FOO, has been defined. In a dynamic context the user might want
to temporarily extend FOO. I will use the name DFLET-METHOD; the user can
write:

(DFLET-METHOD ((FOO ((X C)) ...)) <form>)

and temporarily extend the generic function FOO to have this new method
associated with it during the execution of <form>. This, also, is a
reasonable programming methodology. I was curious about why Gregor thought
I meant something like DFLET-METHOD in my lexical generic function
proposal, even though I think my proposal was relatively clear on my
intention. I believe it is because Gregor thinks in terms of methods and
not in terms of generic functions.  In this long message I have used the
term `generic function' relentlessly, and I have made the distinction
between generic functions and methods clear.

Moon raised the objection that because no one has experience with lexical
generic functions they should not be considered for inclusion as part
of the standard. People have had experience with DEFMETHOD, and people
have had experience with FLET/LABELS. Therefore the combination of them is
not a far-out concept. No one has had experience with meta-objects and
method combination in one system, so should we invoke Moon's design
principle to exclude from consideration a system that has both?

In writing a standard, one tries to take well-known programming language
constructs and methodology and from them make reasonable improvements and
meldings.  Certainly when Common Lisp was being defined some risks were
taken in terms of adopting constructs that few people had experience with.
FLET/LABELS was familiar mostly to Steele and myself; the style of
multiple values adopted was sufficiently unlike others to be considered a
radical departure. The sequence functions were relatively unknown.

Let me relate the tale of TEX. Don Knuth designed TEX in 1977, and TEX78
contained one or two very powerful ideas for typesetting. The power of
these ideas captured the attention of people who care about typesetting
and beautiful manuscripts, to the extent that these people made a major
effort to convert their old documents to TEX.

Over a period of 4 years TEX was in heavy use, and people found that some
of the things they wanted to do were nearly impossible; people also found
that there were various TEX parameters that they wanted to control in
their macros. As with most non-Lisp-like languages, the macro facilities
were horrible.

Because Knuth adopted the design principle of retaining the existing
structure of TEX78 while taking strong consideration of the comments of
his loyal users, he decided to simply re-write TEX *adding* every facility
that was requested. There were approximately 200 of these facilities
added.  Rather than sitting back and thinking about what these critiques
meant - all suggestions for improvments are really critiques - and
re-designing TEX, he just added them to TEX with minimal structural
changes. In fact, the structural changes were mostly those needed to
accomodate the facilities the users requested.

When I hear people state that the overriding design consideration for the
object system is the needs that existing users express or that it is
important to retain a familiar structure while adding a few new facilties,
I am reminded of TEX84, the worst (but most powerful) typesetting language
in existence by far. Yes, we should keep the past firmly in mind, but
not blindly in mind.

/sub
common-lisp-object-system
DEF-GENERIC-OPTIONS

My message - entitled ``Remarks on Generic Functions'' - points out the
primacy of generic functions in this standard. With that in mind, it is
time to discuss the nature of DEFGENERIC. Currently the description of 
DEFGENERIC in the draft document reads:


	   The macro DEFGENERIC defines a generic function and stores it
	   in the symbol function cell of the symbol that is its name.
	   The new generic function object is returned as the result.
	   DEFGENERIC allows you to specify options and declarations that
	   pertain to the generic function as a whole.

The question is whether a DEFGENERIC form on a symbol must be evaluated
before any DEFMETHOD forms can be evaluated on that same symbol.

Here are some reasons why it ought to be required. I will follow that with
some reasons why it ought not be required.

	1. Consider the case of anonymous generic functions. It makes no
	   sense to add methods to a generic function that does not exist.
	   Therefore, a generic function must be created with
	   MAKE-GENERIC (or with a GENERIC-FUNCTION-LABELS) before an
	   ADD-METHOD can be performed on it.  Requiring the evaluation of
	   a DEFGENERIC form before the evaluation of any DEFMETHOD forms
	   creates a parallel situation between the symbol-based generic
	   function case and the anonymous generic function case.

	2. A possible mental model for generic functions and methods is
	   that they are like structures and slots.  It does not make
	   sense to create slots for a structure before a structure is
	   created - it is an absurdity. It makes sense to create the
	   values for those slots, but not the slots themselves.
	   Similarly, with anonymous generic functions it makes sense to
	   create the method functions before the generic function is
	   created, but evaluating the ADD-METHOD forms (or their
	   equivalent) must be done later.

	3. Requiring the evaluation of a DEFGENERIC form before the
	   evaluation of any DEFMETHOD forms enforces a programming style
	   in which important objects - generic functions - are defined
	   before they are modified and used.

Here are reasons why evaluating a DEFGENERIC form before the evaluation of
any DEFMETHOD forms should not be required.

	4. The effect of a series of DEFMETHOD forms followed by a
	   DEFGENERIC form is unambiguous. DEFGENERIC merely modifies some
	   of the options and declarations of the generic function, while
	   generic function creation is a separate event that happens when
	   the first DEFMETHOD form on a particular symbol is evaluated.
	   It is only the case of a DEFGENERIC form being evaluated on a
	   symbol for which there is no existing generic function that is
	   in question; in that case DEFGENERIC creates a generic function
	   first.

	5. The programming style of spreading DEFMETHOD forms throughout
	   various file is encouraged. There is no requirement of loading
	   a `declarations' file full of DEFGENERIC forms. There are no
	   issues to decide regarding the re-loading of the declarartions
	   file.

	6. The case of generic functions and methods is analogous to the
	   case of symbols: There is no requirement to define a symbol
	   before it can be used - simply mentioning the print name of a
	   new symbol will cause that symbol to be created and placed in an
	   appropriate package.

	7. There is nothing to prevent programmers from using a more
	   modular style, putting all DEFGENERIC forms ahead of all
	   DEFMETHOD forms.

If we decide that 4 - 7 prevail, I suggest renaming DEFGENERIC, because
the primary function of DEFGENERIC is to specify options rather than 
to define. I propose DEF-GENERIC-OPTIONS, and the first paragraph
of its specification should read:


	   The macro DEF-GENERIC-OPTIONS allows you to specify options and
	   declarations that pertain to a generic function as a whole.  If
	   there is no generic function associated with the symbol
	   function cell of the symbol that is the name of the generic
	   function, a new generic function object is created and stored
	   in the symbol function cell.  The generic function object is
	   returned as the result.

					-rpg-
Class Precedence List

The class precedence list is a total ordering on the superclasses
of a given class. This list is constrained by the local precedence list
and by the structure of the class lattice above the class in question.
The class precedence list is used to determine, for each instance, from
which classes that instance inherits its slots and behavior.

It is relatively easy for us to decide upon a set of rules that captures
our idea of what the class precedence list should be in all cases. From
those rules it is relatively easy to devise a program that determines
class precedence lists that obey those rules. We say that these rules
are `complete' when, for each class in each class lattice, the rules
determine a unique class precedence list.

The problem seems to be to devise a complete set of rules that also
happens to be easy to present to users.  I believe little thought has been
given to the following consideration. For any set of inheritance
constraints it is possible for a class lattice to be concocted that
satisfies those constraints.  Therefore, it is possibly not important to
devise a set of rules that are complete.  For example, suppose that a set
of rules is devised which admits multiple solutions - there exists a class
in some class lattice such that the inheritance characteristics of that
class are not uniquely determined by the rules - then if the object system
can detect that multiple solutions are possible an error can be signalled
alerting the user that a reformulation of the lattice is necessary.

A second option was recently proposed to me. The rules for determining
the class precedence list can be simple - easy to explain to users - 
but not complete, as long as for any instance variable in an instance it
is possible for the user to state the class from which that instance
variable inherits. Thus, the set of simple rules for inheritance can
be augmented by the user by a set of exceptions of the form, `this
slot comes from this class, etc.' Similarly, the user could state that
some superclass has primacy over others in determining behavior.
\ssect{Number of Namespaces}

There are really a larger number of namespaces than just the two being
discussed here. As we noted earlier, other namespaces include at least
those of blocks, tags, types, and declarations. As such, the names 
\lisp1/ and \lisp2/ that we have been using are slightly misleading. 
The names \lisp5/ and \lisp6/ might be more appropriate.

This being the case, the unification the function and value namespaces
do not accomplish as much as it might initially appear that they do.
Even with that change, the interpretation of a symbol in a Common Lisp
would still depend on the context to disambiguate variables from symbols 
from type names and so on.

On the other hand, some proponents of the change have suggested that,
in time, these other namespaces would be collapsed as well. Dialects of
Scheme have done this -- some to a greater extent than others. 

In fact, however, because of the existence of functions like \smcp{GET}, 
\smcp{ASSOC}, and \smcp{GETHASH} which allow users to effectively associate 
new kinds of information with symbols. The fact that this does not 
affect the complexity of the compiler is more a statement about the 
level of understanding that compilers have than a statement about the 
abstract effect. The truth is that these additional meanings which can 
be associated with symbols can and do have a very powerful effect.

Indeed, much of the power of associative functions like \smcp{GET} derives 
from what amounts to a structured kind of pun -- the fact that a single
symbol (or any object, for that matter) may have more than one kind of
information usefully associated with it. The power and importance of 
this kind of structured interplay between arbitrary namespaces is hard
to deny and probably does not warrant the level of disdain which is 
sometimes given it by Scheme enthusiasts.

/sub
kmp@symbolics
Foobar

I'm not sure what you're saying here:

   Given such a declaration, it would still be possible in a \lisp1/ to write
   definitions such as:

   \begintt
   (DEFUN ZAP (FN X Y)
     (LET ((PLUS (LAMBDA (X Y) (MAPCAR PLUS X Y))))
       (LIST (PLUS (FN X) (FN Y)) (PLUS (FN (FN X)) (FN (FN Y))))))
   \endtt

   \noindent without worrying that the binding of \smcp{PLUS} would affect
   the argument \smcp{FN}.

Now, PLUS was defined using DEFUN earlier, and it was declared GLOBAL.
I take it GLOBAL means that free references to PLUS are to the
GLOBAL definition and that bindings of PLUS are still lexical. So,
the PLUS bound in the LET is to a local, the reference to PLUS in
the body is to the GLOBAL PLUS, and references to PLUS in the body of
the LET are to the local PLUS. So, what does this have to do with FN?

Do you mean that if FN is bound to a function defined like this:

(DEFUN BAZ (X) (PLUS X X))

that the PLUS referred to here has not been altered?

A {\bf namespace} is a sub-environment in which the nature of the objects to
which the location part of a binding may point are restricted to some
subset of all possible objects (not necessarily first-class Lisp objects).
In this white paper, there are two namespaces of concern, which we will
term the `value namespace' and the `function namespace.' Other 
namespaces include  tag names (used by \smcp{TAGBODY} and \smcp{GO}) 
and block names (used by \smcp{BLOCK} and \smcp{RETURN-FROM}), but 
the objects in the location parts of their bindings are not first-class
Lisp objects.
/sub
kmp@symbolics
Moon's Comments

I've tried to take some of Moon's comments to heart. As usual I don't
always agree with him, and I think he uses his reputation as a club
to bully people into doing things they might not otherwise do. This
message is an outline of what I've done to address his comments.

 * "In the terminology section, the definition of ``namespace'' is a bit 
    confused. Restriction of values has nothing to do with namespaces.  
    A namespace is simply a space of bindings of names to values (or 
    more correctly to value-containing locations)."

This is horsehit. It makes me think he didn't take math courses in school.
It's like saying that numbers like 1,2,3... are just reals, so why name them
something different? My definition passed Clinger, whose mathematical
sophistication I regard more highly than Moon's.

I slightly reworded the definitions so that people like Moon will
be less likely to complain.

 * "I don't believe that the current widespread use of the two-namespace
    design is mere slavish imitation of Lisp 1.5.  The historical
    perspective section left me with the impression that that was the
    message it was trying to communicate.  I remember participating in
    several distinct design discussions over the past 13 years, amounting 
    to at least 100 hours in toto, which went into the decision in depth.  
    The conclusion was always to use a two-namespace design.  Admittedly 
    these decisions were always made by groups with a practical orientation
    rather than a theoretical orientation, such as Multics Maclisp group, 
    NIL group, MIT Lisp Machine group, Symbolics 3600 architecture 
    discussions, and Common Lisp design discussions."

I think it largely is choosing to not throw away existing code and
making users rethink their code. Here is Moon's summary of the Symbolics
position in March 1982:

``The only resolution to these issues that Symbolics can accept is to
retain the status quo.''

I'm not sure this reflects deep thinking on the issue by the Common Lisp
group.

In any event, I've slightly expanded that section showing the smooth
transition of `status quo' from Lisp 1.5 to Common Lisp.


 * "The higher-order functions argument and the multiprocessing argument are
    bogus since it has not been demonstrated in the paper that Lisp1 
    encourages functional programming style.  The only section that
    addressed this, `Notational Simplicity', concludes that either notation
    can be considered superior, depending on programmer experience."

They might not be compelling arguments, but they have been raised by
people, so I think it's our responsibility to bring them up.  I think our
treatment is fair, giving these arguments marginal status.

 * "The Number of Namespaces section is somewhat garbled; probably 
    editing errors."

This is the section I couldn't understand, so I think it's ok now.

 * "The arguments in the Macros and Name Collisions section are somewhat
    weakened by all the digressions about copies of compiled code and so
    forth.  The last part of this section could be read as concluding that
    it would be good to change to Lisp1 because it would hasten the
    elimination of macros, which are assumed to be undesirable!  But I
    firmly believe that macros are one of the major reasons Lisp has been
    so successful."

   [I agree with Moon that emphasizing both the present and historical
    significance of macros is probably a good idea. -kmp]

Moon's right here, so I reformulated the section, breaking out the dire
technical parts. I placed a pro-macro section between the name collision
section and the dire technical section.

 * "Especially in connection with the macros hygiene problem, I wish the
    paper had included a section pointing out the folly of standardizing on
    (rather than researching) a language change with known problems and
    no tested solutions.  Something proposed in an obscure thesis that
    no one has seen yet is very different from something that is known to
    work through actual experience in the field."

   [Adding a brief subsection of this form at the end of the technical 
    arguments section would be appropriate and useful. -kmp]

Done.

 * "The space and time efficiency arguments assume particular implementation
    techniques (Lucid's) and the numbers might be very different in other
    implementations.  A better way to look at the time efficiency argument
    is that SETQ of a global variable would be changed from an open-compilable
    operation to a close-compiled operation [in some implementations -kmp]."

I added some equivocation along these lines.

 * "The section titled Special Variables makes an important point, but is
    virtually impenetrable (at least to me).  It should be written more
    clearly.  There should be more discussion of the implications of making
    it illegal to bind the names of globally defined functions (not very
    Scheme-like!).  The argument that Lisp1 would give Common Lisp dynamic
    functional variables for free is bogus; it wouldn't give anything
    that can't be done today with FUNCALL.  What it would really do is
    remove lexical functional variables (the only kind of functional
    variables Common Lisp has), because it would remove functional variables
    entirely.

I've worked with this section a lot. I'll look at it some more. The
thing you get with Lisp1 and dynamic binding is a way to name dynamically
bound functions and use the names like functions.

 * "The Changing Existing Code section is weak.  A reader is likely to
    conclude that there is little problem here, whereas actually the points
    you [kmp] are trying to make are (a) some users would not accept the change,
    and (b) automatic translation is impossible."

I addded some words along these lines.

 * "``The Scheme designers believe that Common Lisp has a number of bad
    warts'' should be expanded.  Does this mean that going to a Lisp1 
    design would not by itself gain any Scheme compatibility, and that 
    it would only be the first in a long parade of incompatible changes 
    that would be necessary before any benefits were derived?  Or does 
    it mean something else?"

I added words to this effect.

 * "The last sentence in the Eulisp section reads like a threat, which is
    probably not what was intended."

I changed this around.

 * "I don't believe the claim that Common Lisp doesn't run on PCs.  I 
    think the future envisioned by the last sentence of this section is
    already here. Also this section fails to explain how changing Common 
    Lisp to Lisp1 would make it run better on small computers.  I doubt
    that the two namespaces are the reason why Common Lisp is as large 
    as it is alleged to be."

I fixed this.

 * "After discussing all these communities, there is one other community
    that ought to be mentioned: the Common Lisp community.  I believe that
    this type of major incompatible change would be likely to split the
    Common Lisp community and return us to the situation we were in before
    the advent of Common Lisp.  This possibility is mentioned briefly but
    deserves additional stress."

   [I agree that adding this would be a good idea. -kmp]

I did this.

 * Moon was disappointed that the paper didn't draw any conclusions.